home
***
CD-ROM
|
disk
|
FTP
|
other
***
search
/
Disc to the Future 2
/
Disc to the Future Part II Programmer's Reference (Wayzata Technology)(6013)(1992).bin
/
MAC
/
SMALLTAL
/
NETCLASS.SM
< prev
next >
Wrap
Text File
|
1990-07-16
|
49KB
|
1,646 lines
"This file consists of a set of Smalltalk/V classes and methods to display and
manipulate a directed acyclic graph i.e. a network of nodes and
links. The code may be used as part of an implementation of,
for example, a browser to display a tree; a project management
(CPM or PERT) network; a computer aided system analysis (CASE)
chart and so on. As usual with Smalltalk, all the source is
provided in this file.
The code has been developed using Digitalk's Smalltalk/V for the
Apple Macintosh, version 1.1. It will probably work with little
modification with PC versions of Smalltalk/V. It will NOT work
without extensive modification with other dialects of Smalltalk
(e.g. Apple Smalltalk-80 and ParkPlace Smalltalk-80).
Availability
============
This code is not in public domain, but it is freely available for
non-commercial use. Use in any military application or by military
personnel is absolutely prohibited. Please distribute this file
widely on BBS etc.
I would be delighted to receive an electronic mail message or
postcard if you find this code interesting or useful. Write
to:
Nigel Gilbert, Social and Computer Sciences Research Group,
University of Surrey, Guildford GU2 5XH, United Kingdom.
Internet: gng@soc.surrey.ac.uk
⌐Nigel Gilbert 1990
About the Network Classes
=========================
The basic classes are:
Network: holds the toplogy (shape) of the network;
NetNode: an individual node, including methods for drawing
a node on the display;
NetLink: an individual link;
NetPane: a Pane which displays the network;
NetDispatcher: a dispatcher which works with a NetPane.
and
NetDemo: implements a trivial application which shows off
the functionality of the these classes.
NetNode implements a basic version of a network node: just a
plain rectangular box. A specialisation of NetNode, NamedNode,
is also included. This implements nodes which have a label
shown in the centre of the rectangle. A specialisation of
NamedNode is also provided, called TextNode. This allows the
user to associate text with the node. The text is displayed
in a text pane below the main network pane when the node is
selected.
There is a specialisation of Network for each kind of NetNode
(Network goes with NetNode, NamedNetwork with NamedNode and
Textnetwork with TextNode. These varieties of Network differ
principally in knowing what class to use to create a new node).
The code is designed so that you can specialise NetNode or its
subclasses in a way that suits your application. For example,
it is easy to add code to make the nodes oval instead of
rectangular in shape.
The demonstration uses the TextNode class.
Running the demonstration
=========================
Evaluate
NetDemo new open.
in the System Transcript window. A window divided into a larger,
top pane and a smaller bottom pane will appear. The top pane is
for displaying the network; the bottom pane is a text editor which
is used to enter and display the details associated with nodes.
To create a new node, click on the upper pane and drag down and
to the right. For further instructions, select the
'About NetDemo...' item on the 'Network' menu in the menu bar.
The Network menu also provides options to save a network in a
file, read a network from a file (the network is added to any
existing network in the display, it does not replace it), 'tidy'
the nodes and change the font of the network labels. The
algorithm used to tidy a network is rather crude; please let me
know if you improve on it.
The NetDemo uses instances of TextNode as nodes. To try out the
other node classes, edit method NetDemo>>net and substitute
Network or NamedNetwork for the existing TextNetwork.
Extensions
==========
To make use of the code, you will need to incorporate it into
your own application. The NetDemo class should be helpful in
showing how it may be added to your own 'model'. You need to
provide at least the following methods in the model class:
accept - if you want to save networks.
net - (or whatever name you specify in the open method)
should answer an instance of the Network class or
of its subclasses.
open - should create a new NetPane and send it the messages
model and name (others are optional).
textPane- needed only if you are using the TextNode nodes.
To create new types of node, you will need to:
- specialise Network to provide a newNode: method to answer
a new instance of the node
- provide a method of that class called fileInNode: to
read details of the node from a file (if you want to
save a network)
- specialise NetNode and provide methods to draw the
node on the display (drawOn:with:width) and to file out
details about the node to a file stream (fileOut:number:)
Note that the latter method is sent with two parameters,
the fileStream to write to and an 'index number' for
the node. The index number is unique to that node and is
used to identify the node when filing data about links
between nodes.
The Network class ensures (in method addLinkFrom:to:) that the user
is only allowed to draw a link between two nodes in one direction
(e.g. if node A has been linked to node B, an attempt to link
node B to node A will be ignored). This method may be specialised
to allow double links or to impose other constraints on links.
Endnote
=======
Please do note alter or remove this text from the file.
-----*****-----
"
Object subclass: #NetLink
instanceVariableNames:
'fromNode toNode '
classVariableNames: ''
poolDictionaries: '' !
!NetLink class methods ! !
!NetLink methods !
distanceTo: aPoint
"answer the perpendicular distance between the link
and aPoint, if aPoint is on a perpendicular to the
link's line"
| a b c m xI yI|
a := Float fromInteger: (toNode centre x - fromNode centre x).
b := Float fromInteger: (toNode centre y - fromNode centre y).
m := b / a.
c := fromNode centre y - (m * fromNode centre x).
"check that the foot of the perpendicular lies on the line"
xI := ((m * (aPoint y - c)) + aPoint x) / (m squared + 1).
(xI < (fromNode centre x min: toNode centre x)) ifTrue: [^ nil].
(xI > (fromNode centre x max: toNode centre x)) ifTrue: [^ nil].
yI := m * xI + c.
(yI < (fromNode centre y min: toNode centre y)) ifTrue: [^ nil].
(yI > (fromNode centre y max: toNode centre y)) ifTrue: [^ nil].
^ ((aPoint y - (m * aPoint x) - c) /
(m squared + 1) sqrt) abs.!
drawOn: aForm with: aMask width: theWidth
"Private - draw the link on aForm using a line of
theWidth pixels"
(Pen new: aForm) mask: aMask; defaultNib: theWidth;
drawFrom: (fromNode centre) to: (toNode centre).!
fileOut: aStream nodes: nodeDictionary
"write out details about the receiver on aStream,
using the nodeDictionary to convert from nodes to
numbers"
aStream nextPutAll: 'link(',
(nodeDictionary
keyAtValue: fromNode
ifAbsent: [self error: 'Node not in dictionary'])
printString, ',',
(nodeDictionary
keyAtValue: toNode
ifAbsent: [self error: 'Node not in dictionary'])
printString, ')'; cr.!
from: aNode to: bNode
"set the receiver to link from aNode to bNode"
fromNode := aNode.
toNode := bNode.!
fromNode
"answer the node the receiver is going from"
^fromNode!
printOn: aStream
"show some details"
aStream nextPutAll: 'NetLink from ',(fromNode centre printString),
' to ', (toNode centre printString).!
selected: aForm
"draw the link in a way which shows that it
has been selected"
self drawOn: aForm with: Form black width: 2.!
toNode
"answer the node the receiver is going to"
^toNode!
unselected: aForm
"draw the link in a way which shows that it
is not selected"
self drawOn: aForm with: Form black width: 1.! !
Object subclass: #NetNode
instanceVariableNames:
'area handles fromLinks toLinks minArea network '
classVariableNames: ''
poolDictionaries: '' !
!NetNode class methods ! !
!NetNode methods !
addFromLink: aLink
"note that there is a link to the receiver"
fromLinks add: aLink!
addToLink: aLink
"note that there is a link from the receiver"
toLinks add: aLink!
area
"answer the area occupied by this node"
^area!
calcHandles
"Private - calculate the rectangles occupied by the
handles attached to the corners of the node outline.
The handles are ordered anticlockwise round the outline."
| centres |
centres := Array with: area origin
with: area origin + (0 @ (area height - 4))
with: area corner - (4 @ 4)
with: area corner - (4 @ area height).
1 to: 4 do: [:corner |
handles at: corner put:
(Rectangle
origin: (centres at: corner)
extent: 4 @ 4)
].
^handles!
centre
"answer the centre of the node's display area"
^area center!
displayDetails: aPane
"by default, a node has no details to display, so do
nothing"!
doubleClick: thePane
"the user has double clicked on the receiver."
self inspect!
drawHandlesOn: aForm
"Private - draw black squares on the four corners of
the outline of the node to show the handles"
self calcHandles.
handles do: [:handle |
(BitBlt destForm: aForm sourceForm: nil)
mask: Form black;
destRect: handle;
copyBits.
]!
drawOn: aForm with: aMask width: theWidth
"Private - display the Receiver as a rectangle,
outlining the shape with the colour aMask,
using an outline of width theWidth "
(BitBlt destForm: aForm sourceForm: nil)
mask: aMask;
destRect: area;
copyBits;
mask: Form white;
destRect: (area insetBy: theWidth);
copyBits.!
drawOutlineOn: aForm
"draw a gray rectangle, using the reverse rule, the
same shape as the node"
(BitBlt destForm: aForm sourceForm: nil)
mask: Form gray;
combinationRule: Form reverse;
destRect: area;
copyBits;
destRect: (area insetBy: 1);
copyBits.!
fileOut: aStream number: myIndexNumber
"write out on aStream the contents of my instance vars"
aStream nextPutAll: 'node(',
myIndexNumber printString,',',
area printString, ')'; cr.!
fromLinks
"answer the set of from links"
^fromLinks!
initialise: aRectangle
"specify the window relative location of the node.
Initialise instance variables. Answer myself"
area := aRectangle.
minArea := 10 @ 10.
handles := Array new: 4.
fromLinks := Set new.
toLinks := Set new.
^self!
inside: aPoint
"answer true if aPoint is inside the outline of the node"
^(area insetBy: 3) containsPoint: aPoint.!
intersects: aNode
"answer true if the receiver's area intersects the
area of aNode"
^ (area intersects: aNode area)!
linkedTo: aNode
"answer true if there is a link between aNode and
the receiver"
aNode toLinks do: [ :link |
link toNode = self ifTrue: [^ true]
].
self toLinks do: [ :link |
link toNode = aNode ifTrue: [^ true]
].
^ false!
moveBy: aPoint
"move the area by aPoint"
area moveBy: aPoint.!
moveToOrigin
"move my area so that its origin is at 0@0"
area moveTo: 0 @ 0.!
net
"answer the network the receiver is linked to"
^ network!
net: aNetwork
"note the network the receiver is linked into"
network := aNetwork!
on: aPoint
"answer true if aPoint is in or near the area occupied
by the node"
^(area expandBy: 1) containsPoint: aPoint!
onCorner: aPoint
"answers true if aPoint is on or near one of the
corners of the outline of the node"
handles do: [ :handle |
((handle expandBy: 2) containsPoint: aPoint)
ifTrue: [^true]].
^false.!
oppositeCorner: aPoint
"answers the point which is opposite aPoint
(a corner of the area in which the node is displayed)"
1 to: 4 do: [:i |
(((handles at: i) expandBy: 2) containsPoint: aPoint)
ifTrue: [
(i = 1) ifTrue: [^ area corner].
(i = 2) ifTrue: [^ (area right @ area top)].
(i = 3) ifTrue: [^ area origin].
(i = 4) ifTrue: [^ (area left @ area bottom)].
].
].
self error: 'aPoint not on a corner'.!
printOn: aStream
"prints a description of the receiver"
aStream nextPutAll: self name, ' at ', self centre printString.!
removeFromLink: aNode
"remove the link from aNode to the receiver"
fromLinks do: [ :link |
link fromNode = aNode
ifTrue: [
fromLinks remove: link.
^link
].
].!
removeToLink: aNode
"remove the link from the receiver to aNode"
toLinks do: [ :link |
link toNode = aNode
ifTrue: [
toLinks remove: link.
^link
].
].!
selected: aForm
"displays the node on aForm in a way that shows it has
been selected"
self drawOn: aForm with: Form gray width: 2.
self drawHandlesOn: aForm.!
shapeTo: aRectangle
"change the area occupied by the receiver to aRectangle,
but do not reduce below minArea.
Answer the new area"
| newArea |
newArea := aRectangle normalise.
(newArea extent >= minArea) ifFalse: [ ^ area := newArea extent: minArea ].
area := newArea.
self calcHandles.
^ area!
storeDetails: aPane
"by default, a node has no details to store, so
do nothing"!
tidyAt: topCorner
"locate myself at topCorner. Then place all my daughters.
Then move myself down so that I am in the middle of my
daughters. Finally, answer my bottom left corner"
| myPos daughterPos dispY|
myPos := topCorner.
dispY := 0.
"if the node has already been placed, put it half way between the
old place and the expected new place"
(area origin y = 0) ifFalse: [
dispY := (myPos y - area origin y) // 2.
myPos := ((area origin x) max: myPos x) @ (area origin y + dispY).
].
toLinks isEmpty ifTrue: [
area moveTo: myPos.
^ (topCorner x @ ((topCorner y max: area bottom) + dispY + 10))
].
daughterPos := (myPos x + area width + 10) @ myPos y.
toLinks do: [ :link |
daughterPos := (link toNode) tidyAt: daughterPos.
].
daughterPos y: (daughterPos y - 10).
area moveTo: ((myPos x) @ ((( myPos y + daughterPos y - area height) // 2) max: myPos y)).
^ (myPos y: (daughterPos y max: area bottom) + dispY + 10).!
toLinks
"answer the set of to links"
^toLinks!
unselected: aForm
"draw the outline of the node in the unselected way"
self drawOn: aForm with: Form black width: 1.! !
NetNode subclass: #NamedNode
instanceVariableNames:
'name '
classVariableNames:
'Font '
poolDictionaries: '' !
!NamedNode class methods !
font: aFont
"set the receiver's class font"
Font := aFont! !
!NamedNode methods !
drawOn: aForm with: aMask width: theWidth
"display the Receiver as a rectangle, outlining the shape
with the colour aMask, using an outline of width theWidth,
and writing my name in the middle "
super drawOn: aForm with: aMask width: theWidth.
(Pen new: aForm)
place: (area center);
centerText: name font: Font.!
fileOut: aStream number: myIndexNumber
"write out on aStream the contents of my instance vars"
aStream nextPutAll: 'node(',
myIndexNumber printString,',',
area printString,',',
name printString, ')'; cr.!
name
"answer my name"
^ name!
name: aString
"set my name and ensure my area is big enough to
display it"
name := aString.
minArea := ((Font stringWidth: aString) + 4) @ (Font height + 4).
area extent: (area extent max: minArea).! !
NamedNode subclass: #TextNode
instanceVariableNames:
'text '
classVariableNames: ''
poolDictionaries: '' !
!TextNode class methods ! !
!TextNode methods !
displayDetails: textPane
"Display the text associated with the receiver in the
text pane"
textPane fileInFrom: text!
fileOut: aStream number: myIndexNumber
"write out on aStream the contents of my instance vars"
aStream nextPutAll: 'node(',
myIndexNumber printString,',',
area printString,',',
text contents printString, ')'; cr.!
initialise: aRectangle
"initialise, giving myself a blank text. Answer myself"
super initialise: aRectangle.
self name: String new.
text := ReadWriteStream on: String new.
^self!
storeDetails: textPane
"recover the text which was displayed in the text
pane (and which may have been changed by the user)"
(textPane contents = text contents)
ifFalse: [
text reset.
textPane fileOutOn: text.
text reset.
self name: (text nextLine).
textPane model changedNet: self with: #newText.
]!
text: aString
"set the receiver's text to aString and reset its name
to the first line of the text"
text reset; nextPutAll: aString; reset.
self name: (text nextLine).! !
GraphDispatcher subclass: #NetDispatcher
instanceVariableNames:
'modified '
classVariableNames: ''
poolDictionaries:
'FunctionKeys CharacterConstants ' !
!NetDispatcher class methods ! !
!NetDispatcher methods !
accept
"Save the modified network. Assumes that saveFile in
the topPane has been preset to a filestream.
Answer true if successful"
| file |
modified ifTrue: [
CursorManager write change.
file := self topDispatcher pane saveFile.
file reOpen; reset.
pane fileOutOn: file.
file flush; truncate; close.
modified := false.
pane topPane label: (file file name); displayLabel.
CursorManager normal change
].
^ true!
initialize
"Private - Initialize the instance variables."
modified := false.
super initialize!
modified
"answer whether my network has been modified since
the last save"
^ modified!
modified: aBoolean
"Change modified to aBoolean."
modified := aBoolean!
processInputKey: aCharacter
"If the character is a Bs (= Delete), send it on to the
pane."
Bs == aCharacter
ifTrue: [^ pane deleteSelection ].
^ super processInputKey: aCharacter.!
processMouseEvent: aCharacter
"Private - Perform the requested function from the
keyboard or mouse. Treats shift + mouse click
just like mouse click"
SelectToFunction == aCharacter
ifTrue: [^ pane selectAtCursor].
super processMouseEvent: aCharacter! !
Object subclass: #Network
instanceVariableNames:
'nodes links '
classVariableNames: ''
poolDictionaries: '' !
!Network class methods !
new
"Create an instance of the receiver and initialize it."
^ super new initialise! !
!Network methods !
add: aNode
"add aNode to the nodes in the network"
nodes add: aNode!
addLinkFrom: nodeA to: nodeB
"answer a new Link if nodeA and nodeB are not already
linked. Disallow a link which is the same as an existing
link, but in the oppposite direction. Ensure that both
nodes are in the network and tell nodeA about the link
to nodeB and vice versa"
| newLink |
nodes add: nodeA; add: nodeB.
(nodeA linkedTo: nodeB) ifTrue: [^ nil].
newLink := self newLink: nodeA to: nodeB.
nodeA addToLink: newLink.
nodeB addFromLink: newLink.
links add: newLink.
^newLink!
deleteLink: aLink
"delete a link from the network and disconnect it from
its to and from nodes"
(aLink toNode) removeFromLink: (aLink fromNode).
(aLink fromNode) removeToLink: (aLink toNode).
links remove: aLink.!
deleteNode: aNode
"delete a node from the network and disconnect it from
its to and from nodes"
aNode toLinks do: [:toLink |
aNode removeToLink: toLink.
(toLink toNode) removeFromLink: aNode.
links remove: toLink. ].
aNode fromLinks do: [:fromLink |
aNode removeFromLink: fromLink.
(fromLink fromNode) removeToLink: aNode.
links remove: fromLink. ].
nodes remove: aNode.!
fileInLink: aStream nodes: nodeDictionary
"read details of a link from aStream, create it
and add it to the network. Numeric references to
nodes are looked up in the dictionary to find actual
nodes"
| link toNode fromNode|
fromNode := nodeDictionary
at: (aStream nextWord asInteger)
ifAbsent: [
self error: 'FromNode not found in dictionary'.
].
toNode := nodeDictionary
at: (aStream nextWord asInteger)
ifAbsent: [
self error: 'ToNode not found in dictionary'.
].
link := self addLinkFrom: fromNode to: toNode.
links add: link.
^ link.!
fileInNode: aStream
"read node details, create a new node and add it to
myself. Answer the node"
| node n1 n2 n3 n4 |
aStream nextWord. "node number"
"get node area"
n1 := aStream nextWord asInteger.
n2 := aStream nextWord asInteger.
aStream nextWord. "corner:"
n3 := aStream nextWord asInteger.
n4 := aStream nextWord asInteger.
node := self newNode: (n1 @ n2 corner: n3 @ n4).
node net: self.
nodes add: node.
^ node!
initialise
"set up the instance variables"
nodes := Set new.
links := Set new.!
links
"answer the links in this network"
^ links!
newLink: nodeA to: nodeB
"answer a new Link. This method may be specialised
to answer different kinds of link"
^ (NetLink new) from: nodeA to: nodeB.!
newNode: aRectangle
"answer a new node, of display area aRectangle.This
method may be specialised to create alternative
nodes"
^ (NetNode new) initialise: aRectangle; net: self.!
nodes
"answer the nodes in the network"
^nodes!
roots
"answers all the nodes with no links pointing to them"
^ nodes select: [ :node | node fromLinks isEmpty]!
setFont: aFont
"set the font used by the receiver's nodes to display
themselves - by default, do nothing"! !
Network subclass: #NamedNetwork
instanceVariableNames: ''
classVariableNames: ''
poolDictionaries: '' !
!NamedNetwork class methods ! !
!NamedNetwork methods !
fileInNode: aStream
"read node details, create a new node and add it to
myself"
| node n1 n2 n3 n4 name |
aStream nextWord. "node number"
n1 := aStream nextWord asInteger.
n2 := aStream nextWord asInteger.
aStream nextWord. "corner:"
n3 := aStream nextWord asInteger.
n4 := aStream nextWord asInteger.
name := aStream nextString.
nodes add: (node := (NamedNode new)
initialise: (n1 @ n2 corner: n3 @ n4);
name: name;
net: self).
^ node!
newNode: aRectangle
"answer a new node, of display area aRectangle.This
method may be specialised to create alternative
nodes"
^ (NamedNode new)
initialise: aRectangle;
name: (WriteStream with:
'Node-', (nodes size printString)) contents;
net: self.!
setFont: aFont
"set the font used by the receiver's nodes to display
themselves"
NamedNode font: aFont! !
NamedNetwork subclass: #TextNetwork
instanceVariableNames: ''
classVariableNames: ''
poolDictionaries: '' !
!TextNetwork class methods ! !
!TextNetwork methods !
fileInNode: aStream
"read node details, create a new node and add it to
myself"
| node n1 n2 n3 n4 text |
aStream nextWord. "node number"
n1 := aStream nextWord asInteger.
n2 := aStream nextWord asInteger.
aStream nextWord. "corner:"
n3 := aStream nextWord asInteger.
n4 := aStream nextWord asInteger.
text := aStream nextString.
nodes add: (node := self newNode: (n1 @ n2 corner: n3 @ n4)).
node text: text.
^ node!
newNode: aRectangle
"answer a new node, of display area aRectangle.This
method may be specialised to create alternative
nodes"
^ (TextNode new)
initialise: aRectangle;
net: self.!
setFont: aFont
"set the font used by the receiver's nodes to display
themselves"
TextNode font: aFont! !
GraphPane subclass: #NetPane
instanceVariableNames:
'selectedLinks nodeStack network displayedNode '
classVariableNames: ''
poolDictionaries: '' !
!NetPane class methods ! !
!NetPane methods !
cancelSelection
"cancel any selection of nodes and links"
selection := Set new.
selectedLinks := Set new.!
changed: nodeOrLink by: action
"tell the model that the network topology has changed"
changeSelector isNil ifFalse: [
model perform: changeSelector
with: nodeOrLink with: action
].!
createNode: aRectangle
"create a new node, of display area aRectangle."
| newNode |
newNode := network newNode: aRectangle.
self changed: newNode by: #created.
^ newNode!
cursorFrom: aPoint with: aRectangle
"answer the position of the cursor, relative to the
pane. The position is constrained so that aRectangle
is always within the formHolder"
| pos insideRect newRectangle |
pos := self windowToPane: (Cursor offset).
insideRect := formHolder boundingBox insetBy: 1.
newRectangle := aRectangle normalise moveBy: (pos - aPoint).
(newRectangle origin x < insideRect origin x)
ifTrue: [pos x: (pos x - (newRectangle origin x - insideRect origin x))]
ifFalse:[
(newRectangle corner x > insideRect corner x)
ifTrue: [pos x: (pos x - (newRectangle corner x - insideRect corner x))].
].
(newRectangle origin y < insideRect origin y)
ifTrue: [pos y: (pos y - (newRectangle origin y - insideRect origin y))]
ifFalse:[
(newRectangle corner y > insideRect corner y)
ifTrue: [pos y: (pos y - (newRectangle corner y - insideRect corner y))].
].
^ pos!
deleteSelection
"remove whatever is selected, if anything"
selection do: [:node |
self unDisplayNodeDetails.
nodeStack remove: node.
selection remove: node.
network deleteNode: node.
self changed: node by: #deleted.
].
selectedLinks do: [ :link |
network deleteLink: link.
selectedLinks remove: link.
self changed: link by: #deleted.
].
self draw!
displayNodeDetails: aNode
"if aNode is the only node selected, display its details
on the text pane, first updating the details of the
previously displayed node in case the user has edited them"
(selection size = 1)
ifFalse: [self unDisplayNodeDetails]
ifTrue: [
(aNode = displayedNode) ifTrue: [^ nil].
aNode isNil ifFalse: [
self unDisplayNodeDetails.
aNode displayDetails: self model textPane.
displayedNode := aNode.
].
].!
doubleClickInNode: aNode at: aPoint
"the user has double clicked inside aNode"
aNode doubleClick: self!
draw
"draw the network, links first, then the nodes"
formHolder white.
self
drawAllLinks;
drawAllNodes;
redraw.!
drawAllLinks
"draw lines representing the links between nodes on the
display"
nodeStack do: [ :fromNode |
(fromNode toLinks) do: [ :toLink |
self drawLink: toLink]
].!
drawAllNodes
"draw all the nodes on the display.Note
that they must be drawn in order, bottom first"
nodeStack do: [ :node | self drawNode: node ]!
drawLink: aLink
"draw the link, either selected or unselected, according
to its current setting"
(selectedLinks includes: aLink)
ifTrue: [aLink selected: formHolder]
ifFalse: [aLink unselected: formHolder].!
drawNode: aNode
"draw the node, either selected or unselected, according
to its current setting"
(selection includes: aNode)
ifTrue: [aNode selected: formHolder]
ifFalse: [aNode unselected: formHolder].!
fileIn
"file in a network and display it. Answer true if
successful"
| fStream |
(fStream := SFReply getTextFile) isNil ifTrue: [^ nil].
self fileIn: fStream.
fStream close.
self topPane saveFile isNil
ifTrue: [(self topPane)
saveFile: fStream;
label: fStream file name;
displayLabel ].
self dispatcher modified: true.
^ true!
fileIn: aStream
"read nodes and links from aStream "
| word nodeDictionary index|
nodeDictionary := IdentityDictionary new.
index := 0.
[aStream atEnd] whileFalse: [
word := aStream nextWord.
(word = 'node') ifTrue: [
nodeDictionary at: index put:
(network fileInNode: aStream).
index := index + 1.
].
(word = 'link') ifTrue: [
network fileInLink: aStream nodes: nodeDictionary.
]
].
nodeStack := network nodes asOrderedCollection.
self cancelSelection;
draw.!
fileOutOn: aStream
"write out all the nodes and links in a form in which they
can be read in again"
| nodeDictionary index |
nodeDictionary := IdentityDictionary new.
index := 0.
network nodes do: [ :node |
nodeDictionary at: index put: node.
node fileOut: aStream number: index.
index := index + 1.
].
network links do: [ :link |
link fileOut: aStream nodes: nodeDictionary.
].!
findNode: aPoint
"answer the node which is displayed at aPoint, or
nil if no node is there"
nodeStack reverseDo: [:node |
(node on: aPoint) ifTrue: [ ^node ]
].
^nil!
getLinkFrom: aNode
"get the user to draw a link from the node to
some other one"
|newPoint oldPoint trackingPen destNode lineDisplayed link|
trackingPen := (Pen new: formHolder) combinationRule: Form reverse.
lineDisplayed := false.
oldPoint := aNode centre.
trackingPen place: oldPoint; drawTo: oldPoint.
EventRecord whileMouseDownDo: [
oldPoint = (newPoint := self windowToPane: (Cursor offset))
ifFalse: [
lineDisplayed ifTrue: [trackingPen drawTo: oldPoint].
(aNode inside: newPoint)
ifFalse: [
trackingPen drawTo: newPoint.
oldPoint := newPoint.
lineDisplayed := true.
self redraw.]
ifTrue: [
lineDisplayed ifTrue: [self redraw ].
lineDisplayed := false.].
]
].
trackingPen drawTo: oldPoint.
"if the user has let go over another node, add the link to the network."
newPoint isNil
ifFalse: [ (destNode := self findNode: newPoint) isNil
ifFalse: [ destNode = aNode
ifFalse: [
(link := network addLinkFrom: aNode to: destNode) isNil
ifFalse: [self changed: link by: #linked]
]
]
].!
initialize
"Initialize the drawing area to a suitable size and then
initialise myself."
formHolder := Form new extent: (Screen extent).
selection := Set new.
selectedLinks := Set new.
nodeStack := OrderedCollection new: 0.
self dispatcher: (NetDispatcher new).
super initialize.!
mouseDownAt: aPoint
"The user has pressed the mouse button. Act according to
whether the mouse is on a node or not"
| panePoint node|
panePoint := self windowToPane: aPoint.
(node := self findNode: panePoint) isNil
ifFalse: [ self mouseInNode: node at: panePoint]
ifTrue: [ self mouseNotInNode: panePoint].
self draw.!
mouseInNode: aNode at:aPoint
"depending on where the mouse is in the node,
start drawing a link to another node,
or move the node (or nodes if there are several selected),
or shape the node"
self select: aNode.
(aNode inside: aPoint)
ifTrue: [
Terminal underDoubleClickDelay
ifTrue: [ self doubleClickInNode: aNode at: aPoint.]
ifFalse: [self getLinkFrom: aNode]
]
ifFalse: [
(aNode onCorner: aPoint)
ifTrue: [self shapeNode: aNode from: aPoint]
ifFalse:[self moveNode: aPoint]
].
self displayNodeDetails: aNode.!
mouseNotInNode: aPoint
"the user has pressed the mouse button while not on a
node. If the mouse is near a link, select it. If not,
if the user then drags, create a new node and
add it to the network"
| box node link|
((link := self selectLink: aPoint) notNil) ifTrue: [
"user has selected a link"
^ link
].
(box := self promptForRectangle: aPoint) = nil
ifFalse: [
node := self createNode: box.
network add: node.
nodeStack addLast: node.
self select: node;
displayNodeDetails: node.
]
ifTrue: [self unDisplayNodeDetails ].!
moveNode: aPoint
"move the selection"
| oldPoint newPoint rectDisplayed |
rectDisplayed := false.
oldPoint := aPoint.
EventRecord whileMouseDownDo: [
oldPoint = (newPoint :=
self cursorFrom: oldPoint with: (self selectedArea))
ifFalse: [
selection do: [:node |
rectDisplayed ifTrue: [node drawOutlineOn: formHolder].
node moveBy: (newPoint - oldPoint).
node drawOutlineOn: formHolder.
].
rectDisplayed := true.
self redraw.
oldPoint := newPoint.
]
].!
open
"set up the network, returned by the model"
network := model perform: name.
network setFont: curFont.!
promptForRectangle: origin
"answer a rectangle as suggested by the user, or nil if the
user gives up by making the rectangle smaller than the default"
| initialRect rect pen corner newCorner rectDisplayed |
initialRect := origin extent: 10 @ 10.
corner := initialRect corner.
rect := initialRect copy.
pen := (Pen new: formHolder) combinationRule: Form reverse; gray.
rectDisplayed := false.
EventRecord whileMouseDownDo: [
corner = (newCorner := self cursorFrom: corner with: rect)
ifFalse: [
((newCorner x < initialRect corner x) or:
[newCorner y < initialRect corner y])
ifTrue: [
"(still) in initial rectangle"
rectDisplayed ifTrue: [
pen drawRectangle: rect.
rectDisplayed := false.
CursorManager normal change.
]
]
ifFalse: [
rectDisplayed
ifFalse: [ CursorManager hair change.]
ifTrue: [ pen drawRectangle: rect].
rect origin: origin corner: newCorner.
pen drawRectangle: rect.
rectDisplayed := true.
self redraw.
].
corner := newCorner.
] "cursor moved"
]. "whileMouseDown"
rectDisplayed ifTrue: [
pen drawRectangle: rect.
CursorManager normal change.
^rect].
^nil!
redraw
"redisplay the window, by copying the form in
formHolder onto it"
self show: (formHolder boundingBox)!
release
"release the instance variables"
selectedLinks := nodeStack := network := nil.
super release!
save
"Save the contents of the pane. Answer true if successful"
(self topPane saveFile) isNil
ifTrue: [^ self saveAs: 'Network']
ifFalse: [^ self dispatcher accept].!
saveAs: defaultFileName
"Save the contents of the panes to a file, offering
the defaultFileName. Answer true if successful"
| file topPane|
topPane := self topPane.
file := SFReply putFile:
((file := topPane saveFile) isNil
ifTrue: [ defaultFileName ]
ifFalse: [ file file name ]).
file isNil ifTrue: [ ^ false ].
file close.
topPane saveFile: file.
(self dispatcher modified: true; accept) ifFalse: [ ^ false].
^ true!
select: aNode
"if aNode is already selected, do nothing.
if the shift key is not down, cancel any existing
selection. Then add aNode to the selection"
(selection includes: aNode) ifTrue: [^ nil].
(CurrentEvent isShift) ifFalse: [ self cancelSelection ].
selection add: aNode.
"move node to top of display stack"
nodeStack remove: aNode; addLast: aNode.
self draw.!
selectAtCursor
"the user has press a mouse button. Do something"
self mouseDownAt: (Cursor offset)!
selectedArea
"answer the smallest area which entirely encloses
the outline of all the nodes currently selected.
Assumes that at least one node is selected"
| area |
area := (selection asArray at: 1) area.
selection do: [ :node |
area := area merge: (node area)].
^area.!
selectLink: aPoint
"if aPoint is near a link, make it the selected link,
or add it to the selected links if the shift key is down"
| d |
(CurrentEvent isShift) ifFalse: [ self cancelSelection ].
network links do: [:link |
d := link distanceTo: aPoint.
d isNil ifFalse: [
(d < 5) ifTrue: [
(selectedLinks includes: link) ifFalse: [
selectedLinks add: link.
self draw.
^link
]
]
]
].
^nil.!
setFont
"reset the font for displaying nodes"
| font |
font := Dialog setFont: curFont message: 'Select Font:'.
font isNil ifTrue: [ ^ self ].
curFont := font.
network setFont: font.
nodeStack do: [:node | node name: (node name)].
self draw!
shapeNode: aNode from: aPoint
"reshape aNode, by dragging the corner near aPoint"
| oldPoint newPoint origin rect rectDisplayed|
rectDisplayed := false.
oldPoint := aPoint.
origin := aNode oppositeCorner: aPoint.
rect := aNode area.
EventRecord whileMouseDownDo: [
oldPoint = (newPoint := self cursorFrom: oldPoint with: rect)
ifFalse: [
rect := origin corner: newPoint.
rectDisplayed
ifFalse: [
"only one node can be shaped at a time"
selection size = 1 ifFalse: [self cancelSelection; select: aNode.]
]
ifTrue: [aNode drawOutlineOn: formHolder].
rect := aNode shapeTo: rect.
aNode drawOutlineOn: formHolder.
rectDisplayed := true.
self redraw.
oldPoint := newPoint.
]
].!
tidy
"re-arrange the nodes so that they are tidily positioned"
| rootPos |
nodeStack do: [ :node | node moveToOrigin].
rootPos := 10 @ 10.
network roots do: [ :root |
rootPos y: (root tidyAt: rootPos) y + 10.
].
self draw.!
topCorner: aPoint
"Change topCorner to aPoint, but don't allow any
area beyond the form to become visible."
topCorner := aPoint max: 0@0.
((topCorner x + frame width) > formHolder width)
ifTrue: [topCorner x: (formHolder width - frame width)].
((topCorner y + frame height) > formHolder height)
ifTrue: [topCorner y: (formHolder height - frame height)].
self
show: (topCorner extent: frame extent);
changed: #scroll.!
totalLength
"Answer a length used to calculate the ratio of the visible
to the invisible parts of the form, for positioning the
scroll thumb."
^ (formHolder height - frame height)!
totalWidth
"Answer a width used to calculate the ratio of the visible
to the invisible parts of the form, for positioning the
scroll thumb."
^ (formHolder width - frame width)!
unDisplayNodeDetails
"if there are node details on display, re-store them
in the node and blank the text pane"
| textPane |
displayedNode isNil ifTrue: [^nil].
textPane := self model textPane.
displayedNode storeDetails: textPane.
displayedNode := nil.
textPane
selectAll;
replaceWithChar: $ ;
showWindow.!
update: aParameter
"note that something has changed"
self dispatcher modified: true.!
windowToPane: aPoint
"aPoint is in window relative coordinates. Answer the
point in pane relative coordinates"
^aPoint + self topCorner - self frame origin! !
Object subclass: #NetDemo
instanceVariableNames:
'topPane netPane textPane '
classVariableNames: ''
poolDictionaries:
'SystemMenus ' !
!NetDemo class methods ! !
!NetDemo methods !
about
"display a window with a brief description of this
demonstration"
('About NetDemo...\',
'This demonstrates a set of Smalltalk/V classes and methods\',
'for displaying and manipulating directed acyclic graphs i.e.\',
'nodes and the links between them.\\',
'Using the Demonstration:\',
'To create a node, click on the top, larger window. Then\',
' drag down and to the right.\',
'To destroy a node, click on the node (to select it) and press\',
' the delete key.\',
'To select a node, click anywhere inside it.\',
'To select several nodes, hold down the shift key while selecting\',
' each one in turn.\',
'To deselect a node or nodes, click anywhere in the display\',
' window except on a node.\',
'To label a node, click in the node and then click in the bottom\',
' window. Type as many lines of "details" about the node as\',
' you wish. Then click in the upper window, away from the\',
' node. The first line of the details will be copied into\',
' the node as its label.\',
'To show a node''s details in the lower, text window, select the\',
' node in the upper, display window\',
'To move a node, click anywhere on the edge of the node except at\',
' a corner to select it, and drag it to where you want it to\',
' go.\',
'To reshape a node, click on one of the corners (on the black\',
' "handles") and drag. You can''t make the node smaller than\',
' a reasonable size.\',
'To draw a link between two nodes, click in the centre of one node\',
' and drag towards the centre of the other node. If you\',
' let go of the mouse button before you reach another node,\',
' no link is made.\',
'To select a link, click on it.\',
'To delete a link, select it and press the delete key.\',
' \',
'The basic classes are:\',
'Network: which holds the toplogy (shape) of the network;\',
'NetNode: an individual node, including methods for drawing\',
' a node on the display;\',
'NetLink: an individual link;\',
'NetPane: a Pane which displays the network;\',
'NetDispatcher: a dispatcher which works with a NetPane.\')
breakLinesAtBackSlashes edit.!
accept
"save the network. Answer true if successful"
^ netPane save!
changedNet: nodeOrLink with: action
"invoked by the pane when the user changes the
topology of the network"
(topPane menuBar menuAt: 'Network') enable: #save.
self changed: nodeOrLink!
close
"close down"
topPane dispatcher closeIt.!
fileIn
"open and read a file containing nodes and links"
netPane fileIn!
fileOut
"save the current network into a specified file"
(netPane saveAs: 'Network') ifTrue: [
(topPane menuBar menuAt: 'Network') disable: #save
].!
net
"answer the data of the pane: the network which it is
to show. To use a different class of network and
corresponding nodes, just change the class specified
below. Everything else changes to suit."
^ (TextNetwork new)!
netFont
"get a new font for displaying the nodes
from the user"
netPane setFont.!
netMenu
"answer my menu"
^ (Menu labels:
'File In...\Save/S\File Out...\Tidy/T\Net Font...\Close/W\About NetDemo...'
breakLinesAtBackSlashes
lines:
#(1 3 5 6)
selectors:
#(fileIn save fileOut tidy netFont close about))
title: 'Network'!
open
"open the Network menu in the menubar and a default
blank display window"
topPane := TopPane new
label: 'Untitled';
model: self.
topPane addSubpane:
(netPane := NetPane new
model: self;
name: #net;
menu: #netMenu;
change: #changedNet:with:;
framingRatio: (0 @ 0 extent: 1 @ (3/4))).
topPane addSubpane:
(textPane := TextPane new
model: self;
name: #text;
framingRatio: (0 @ (3/4) extent: 1 @ (1/4))).
topPane dispatcher open scheduleWindow.!
save
"save the current network into the current file"
(self accept) ifTrue: [
(topPane menuBar menuAt: 'Network') disable: #save
].!
text
"Initialise the text pane to nothing"
^String new!
textPane
"answer the window's text pane"
^ textPane!
tidy
"tidy the network"
netPane tidy! !
!Rectangle methods !
normalise
"answer a rectangle at the same location and with the
shape as self, but with the origin at the top left corner"
^ ((origin x) min: (corner x)) @ ((origin y) min: (corner y))
extent: self extent abs.! !
!Stream methods !
nextString
"Answer a String containing the next string in the
receiver stream. A string is a sequence of characters begun
and ended with $'. Two adjacent $' are treated as one embedded
$', not as a string terminator."
| answer |
[self atEnd ifTrue: [^ String new].
self next = $']
whileFalse: [].
answer := self upTo: $'.
[self atEnd or: [(self peekFor: $') not]]
whileFalse: [
answer := answer,
(String with: $'),
(self upTo: $')].
^ answer! !